KeyIsPresent Function

public function KeyIsPresent(key, iniDB, section, subSection) result(isHere)

return true if key is present, false otherwise

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: key
type(IniList), intent(in) :: iniDB
character(len=*), intent(in), optional :: section
character(len=*), intent(in), optional :: subSection

Return Value logical


Variables

Type Visibility Attributes Name Initial
integer(kind=long), public :: elmBegin
integer(kind=long), public :: elmEnd
integer(kind=long), public :: i

Source Code

FUNCTION KeyIsPresent &
!
(key, iniDB, section, subSection) &
!
RESULT (isHere)

IMPLICIT NONE

! subroutine arguments 
! Scalar arguments with intent(in):
CHARACTER (LEN = *),           INTENT(IN) :: key
TYPE (IniList)     ,           INTENT(IN) :: iniDB
CHARACTER (LEN = *), OPTIONAL, INTENT(IN) :: section
CHARACTER (LEN = *), OPTIONAL, INTENT(IN) :: subSection

! Local Scalars: 
LOGICAL :: isHere
INTEGER (KIND = long) :: elmBegin
INTEGER (KIND = long) :: elmEnd
INTEGER (KIND = long) :: i
!------------end of declaration------------------------------------------------

IF ( PRESENT (section) .AND. PRESENT (subSection) ) THEN
 CALL Sync(elmBegin, elmEnd, iniDB, sec = section, subSec = subSection)
ELSE IF ( PRESENT (section) .AND. .NOT.PRESENT (subSection)) THEN
	CALL Sync(elmBegin, elmEnd, iniDB, sec = section)
ELSE
	CALL Sync(elmBegin, elmEnd, iniDB)
ENDIF

isHere = .FALSE.

DO i = elmBegin, elmEnd
   IF (Key == iniDB % Keys(i) ) THEN
      isHere = .TRUE.
      RETURN
   END IF
END DO

END FUNCTION KeyIsPresent